home *** CD-ROM | disk | FTP | other *** search
/ Libris Britannia 4 / science library(b).zip / science library(b) / COMMUNIC / 1572B.ZIP / KMT_IBM4.ZIP / MSSCOM.ASM < prev    next >
Assembly Source File  |  1989-07-11  |  57KB  |  1,218 lines

  1.         NAME    msscom
  2. ; File MSSCOM.ASM
  3. ; Edit history:
  4. ; Last edit 21 Nov 1988
  5. ; 21 Nov 1988 Version 2.32
  6. ; 21 August 1988 Wait for char in recv'd EOL position but accept all but SOH.
  7. ; 1 July 1988 Version 2.31
  8. ; 27 Feb 1988 Add capability of stdin being a file. [jrd]
  9. ; 1 Jan 1988 version 2.30
  10.  
  11.         public  data, spack, rpack, portval, port1, port2, port3, port4, hierr
  12.         public  prtbase, nports, sleep, spause
  13.         include mssdef.h
  14.  
  15. biostod equ     1ah             ; Bios time of day tic routine
  16. stat_suc equ    0               ; success
  17. stat_tmo equ    1               ; timeout
  18. stat_chk equ    2               ; checksum mismatch
  19. stat_ptl equ    4               ; packet too long
  20. stat_int equ    8               ; user interrupt
  21. stat_eol equ    10h             ; eol char seen
  22.  
  23. datas   segment public 'datas'
  24.         extrn   flags:byte, trans:byte, pack:byte, fsta:word, fmtdsp:byte
  25.  
  26. prtbase label   byte
  27. port1   prtinfo <0FFFH,0,defpar,1,0,defhand,floxon>
  28. port2   prtinfo <0FFFH,0,defpar,1,0,defhand,floxon>
  29. port3   prtinfo <0FFFH,0,defpar,1,0,defhand,floxon>
  30. port4   prtinfo <0FFFH,0,defpar,1,0,defhand,floxon>
  31.         rept    portmax-4
  32.         prtinfo <0FFFH,0,defpar,1,0,defhand,floxon>
  33.         endm
  34.  
  35. ;; systems with two ports can set portval to port1 or port2.
  36. ;; systems with more than two ports can set nports higher,
  37. ;; then set portval to the address prtbase+(#-1)*size prtinfo
  38. ;; where # is the desired port.
  39.  
  40. portval dw      port1           ; Default is to use port 1.
  41. nports  db      2               ; # of known ports
  42. hierr   db      0               ; Non-ascii char (non-zero if yes).
  43. parmsk  db      0ffh            ; parity mask (0FFH for 8bit data path) [umd]
  44. spmes   db      'Spack: $'
  45. rpmes   db      'Rpack: $'
  46. crlf    db      cr,lf,'$'
  47. cemsg   db      'User intervention$'
  48.  
  49. sixzero dw      60              ; for div operation in rec packet timeouts
  50. ninefive dw     95              ; for mult/div with long packets
  51. temp    dw      0
  52. tmp     db      0
  53. linecnt dw      0               ; debug line width counter
  54. spause  db      0               ; # millisec to wait before sending pkt
  55. prvtyp  db      0               ; Type of last packet sent
  56. pktptr  dw      0               ; Position in receive packet.
  57. chksum  dw      0               ; running checksum (two char)
  58. chrcnt  dw      0               ; number of bytes in data field of a packet
  59. status  dw      0               ; status of packet receiver (0 = ok)
  60. pktype  db      0               ; received packet TYPE holding area
  61. debflg  db      0               ; debug display, send/receive flag
  62. tmpflg  db      0               ; flags.cxzflg at entry to rpack
  63. timeit  db      0               ; arm timeout counter
  64. fairflg dw      0               ; fairness flag, for console/port reads.
  65. time    dw      2 dup (0)       ; Sleep, when we should timeout.
  66. rptim   db      4 dup (0)       ; read packet timeout slots
  67. spkcnt  dw      0               ; number of bytes sent in this packet
  68. rpkcnt  dw      0               ; number of bytes received in this packet
  69.  
  70.                                 ; Prolog, Data, Trailer must be kept together
  71. prolog  db      8 dup (?)       ; Packet header (SOH, LEN, SEQ, TYPE, xlen)
  72. data    db      maxpack+10 dup (?) ; Data field of packet (used in many places)
  73.                                 ; checksum, eol, handshake + null term
  74. datas   ends
  75.  
  76. code    segment public 'code'
  77.         extrn   prtchr:near, clrbuf:near, outchr:near, isdev:near
  78.         extrn   sppos:near, stpos:near, biterr:near, intmsg:near
  79.         extrn   clearl:near, rppos:near, errpack:near, prtscr:near
  80.         extrn   pktcpt:near, strlen:near, pcwait:near
  81.  
  82.         assume  cs:code, ds:datas
  83.  
  84. ;       Packet routines
  85.  
  86. ; Send_Packet
  87. ; This routine assembles a packet from the arguments given and sends it
  88. ; to the host.
  89. ;
  90. ; Expects the following:
  91. ;       AH     - Type of packet (D,Y,N,S,I,R,E,F,Z,other)
  92. ;       PACK.SEQNUM - Packet sequence number
  93. ;       PACK.DATLEN - Number of data characters
  94. ; Returns: +1 always
  95. ; Packet construction areas:
  96. ;       Prolog (8 bytes)                        Data     null  Data
  97. ;+----------------------------------------+---------------+---------------+
  98. ;| SOH,LEN,SEQ,TYPE,Xlen(2-3),Xlen chksum | packet's data | chksum,EOL,HS |
  99. ;+----------------------------------------+---------------+---------------+
  100. ; where Xlen is 2 byte (Long) or 3 byte (Extra Long) count of bytes to follow.
  101. ;
  102. SPKT    PROC    NEAR
  103.  
  104. spack:  push    ax              ; save packet type (in ah)
  105.         call    clrbuf          ; clear serial port input buffer
  106.         call    prtchr          ; exercise receiver
  107.          nop
  108.          nop
  109.          nop
  110.         call    clrbuf          ; clear serial  port input buffer
  111.         mov     spkcnt,0        ; number of bytes sent in this packet
  112.         add     fsta.pspkt,1    ; statistics, count a packet being sent
  113.         adc     fsta.pspkt+2,0  ;  ripple carry
  114.         mov     al,spause       ; Wait spause milliseconds before
  115.         xor     ah,ah           ;   sending a packet
  116.         or      al,al           ; zero?
  117.         jz      spk1            ; z = yes
  118.         call    pcwait          ;   to let other side get ready
  119. spk1:   mov     dh,trans.spad   ; Get the number of padding chars.
  120. spk2:   dec     dh
  121.         cmp     dh,0
  122.         jl      spk5            ; If none left proceed.
  123.         mov     ah,trans.spadch ; Get the padding char.
  124.         push    dx              ; save loop counter
  125.         call    outchr          ; Output it.
  126.          jmp    spk3            ; failed
  127.          nop                    ; must be three bytes
  128.         pop     dx              ; get loop counter
  129.         jmp     spk2            ; do remaining padding chars
  130. spk3:   pop     dx
  131.         pop     ax
  132.         ret                     ; failed
  133.  
  134. spk5:   pop     ax              ; recover ah
  135.         mov     prvtyp,ah       ; Remember packet type
  136.         mov     bx,portval      ; Get current port structure [umd]
  137.         mov     parmsk,0ffh     ; Set parity mask for 8 bits [umd]
  138.         cmp     [bx].parflg,parnon      ; Using parity? [umd]
  139.         je      spacka          ; e = no. use mask as is. [umd]
  140.         mov     parmsk,7fh      ; else set mask for 7 data bits. [umd]
  141. spacka: call    snddeb          ; do debug display (while it's still our turn)
  142.         mov     pktptr,offset prolog
  143.         mov     word ptr prolog,0
  144.         mov     word ptr prolog+2,0
  145.         mov     word ptr prolog+4,0
  146.         mov     word ptr prolog+6,0
  147.         mov     al,trans.ssoh   ; Get the start of header char.
  148.         mov     prolog,al       ; Put SOH in the packet.
  149.         mov     ax,pack.seqnum  ; SEQ
  150.         add     al,20h          ; ascii bias
  151.         mov     prolog+2,al     ; store SEQ in packet
  152.         mov     ah,0
  153.         mov     chksum,ax       ; start checksum
  154.         mov     al,prvtyp       ; TYPE
  155.         mov     prolog+3,al     ; store TYPE
  156.         add     chksum,ax       ; add to checksum
  157. ;
  158. ; packet length type is directly governed here by length of header plus data
  159. ; field, pack.datlen, plus chksum: regular <= 94, long <= 9024, else X long.
  160. ;
  161.         mov     ax,pack.datlen  ; DATA length
  162.         add     ax,2            ; add SEQ, TYPE lengths
  163.         add     al,trans.chklen ; add checksum length at the end
  164.         adc     ah,0            ; propagate carry, yields overall new length
  165.         cmp     ax,maxpack      ; too big?
  166.         jle     spdlp0          ; le = ok
  167.         ret                     ; return bad
  168. spdlp0:
  169.         mov     pack.lentyp,3   ; assume regular packet
  170.         cmp     ax,94           ; longer than a regular?
  171.         ja      spdlp1          ; a = use long
  172.         add     al,20h          ; convert length to ascii
  173.         mov     prolog+1,al     ; store LEN
  174.         mov     ah,0
  175.         add     chksum,ax       ; add LEN to checksum
  176.         jmp     spklp5          ; do regular
  177. spdlp1: push    ax              ; Use Long packets (type 3)
  178.         push    bx
  179.         push    cx
  180.         push    dx
  181.         sub     ax,2            ; deduct SEQ and TYPE from above = data+chksum
  182.         mov     pack.lentyp,0   ; assume type 0 packet
  183.         cmp     ax,(95*95-1)    ; longest type 0 packet (9024)
  184.         jbe     spdlp3          ; be = type 0
  185.         mov     pack.lentyp,1   ; type 1 packet
  186. spdlp3: mov     bl,pack.lentyp  ; add new LEN field to checksum
  187.         add     bl,20h          ; ascii bias, tochar()
  188.         mov     bh,0
  189.         add     chksum,bx       ; add to running checksum
  190.         mov     prolog+1,bl     ; put LEN into packet
  191.         mov     bx,offset prolog+4      ; address of extended length field
  192.         mov     cx,1            ; a counter
  193.         xor     dx,dx           ; high order numerator of length
  194. spdlp7: div     ninefive        ; divide ax by 95. quo = ax, rem = dx
  195.         push    dx              ; push remainder
  196.         inc     cx              ; count push depth
  197.         cmp     ax,95           ; quotient >= 95?
  198.         jae     spdlp7          ; ae = yes, recurse
  199.         push    ax              ; push for pop below
  200. spdlp8: pop     ax              ; get a digit
  201.         add     al,20h          ; apply tochar()
  202.         mov     [bx],al         ; store in data field
  203.         add     chksum,ax       ; accumulate checksum for header
  204.         inc     bx              ; point to next data field byte
  205.         mov     byte ptr[bx],0  ; insert terminator
  206.         loop    spdlp8          ; get the rest
  207.                                 ;
  208.         mov     ax,chksum       ; current checksum
  209.         shl     ax,1            ; put two highest bits of al into ah
  210.         shl     ax,1
  211.         and     ah,3            ; want just those two bits
  212.         shr     al,1            ; put al back in place
  213.         shr     al,1
  214.         add     al,ah           ; add two high bits to earlier checksum
  215.         and     al,03fh         ; chop to lower 6 bits (mod 64)
  216.         add     al,20h          ; apply tochar()
  217.         mov     [bx],al         ; store that in length's header checksum
  218.         mov     ah,0
  219.         add     chksum,ax       ; add that byte to running checksum
  220.         pop     dx
  221.         pop     cx
  222.         pop     bx
  223.         pop     ax
  224.  
  225. spklp5: push    si      ; assume soh, len, seq, type, extra len are in prolog
  226.         push    di
  227.         push    cx
  228.         push    ds
  229.         pop     es              ; set es to data segment for implied es:di
  230.         mov     si,offset prolog        ; source
  231.         mov     di,offset data-1        ; end point of destination
  232.         mov     pktptr,offset data      ; start of packet ptr for debug
  233.         cmp     pack.lentyp,0   ; long packets?
  234.         jne     spklp6          ; ne = no
  235.         add     si,6            ; long packets
  236.         mov     cx,7            ; seven bytes soh,len,seq,type, xl1,xl2,xlchk
  237.         jmp     spklp8
  238. spklp6: cmp     pack.lentyp,1   ; extra long packets?
  239.         jne     spklp7          ; ne = no
  240.         mov     cx,8            ; extra long packets
  241.         add     si,7
  242.         jmp     spklp8
  243. spklp7: add     si,3            ; regular packets, slide up by four bytes
  244.         mov     cx,4            ; number of bytes to move
  245. spklp8: jcxz    spklp9          ; no movement needed
  246.         sub     pktptr,cx       ; pktprt=new offset of prolog section
  247.         std
  248.         rep     movsb           ; move the protocol header, cx times
  249.         cld
  250. spklp9: pop     cx
  251.         pop     di
  252.         pop     si
  253.         mov     bx,pktptr       ; place where protocol section starts
  254. spklp10:mov     ah,[bx]         ; protocol part
  255.         inc     bx
  256.         call    spkout          ; send byte to serial port
  257.         jnc     spklp11         ; nc = good send
  258.         jmp     spackq          ; bad send
  259. spklp11:cmp     bx,offset data  ; done all protocol parts yet?
  260.         jb      spklp10         ; b = not yet
  261.         mov     bx,offset data  ; select from given data buffer
  262.         mov     dx,pack.datlen  ; Get the number of data bytes in packet.
  263. spack2: dec     dx              ; Decrement the char count.
  264.         js      spack3          ;  sign = no, finish up.
  265.         mov     al,byte ptr[bx] ; get a data char
  266.         inc     bx              ; point to next char [umd]
  267.         test    al,80h          ; eighth bit set?
  268.         jz      spackb          ; z = no
  269.         and     al,parmsk       ; apply parity mask, may clear 8th bit [umd]
  270.         cmp     hierr,0         ; printed high bit error yet? [umd]
  271.         jne     spackb          ; ne = yes [umd]
  272.         push    ax
  273.         push    bx
  274.         push    cx
  275.         push    dx
  276.         call    biterr
  277.         pop     dx
  278.         pop     cx
  279.         pop     bx
  280.         pop     ax
  281.         mov     hierr,0FFH      ; set err flag.
  282. spackb: mov     ah,0
  283.         add     chksum,ax       ; add the char to the checksum [umd]
  284.         and     chksum,0fffh    ; keep only low order 12 bits
  285.         mov     ah,al           ; put char in ah where spkout wants it
  286.         call    spkout          ; send it
  287.         jnc     spack2          ; Go get more data chars
  288.         jmp     spackq          ; bad send
  289.  
  290. spack3: mov     cx,chksum
  291.         cmp     trans.chklen,2  ; What kind of checksum are we using?
  292.         je      spackx          ; e = 2 characters.
  293.         jg      spacky          ; g = 3 characters.
  294.         mov     ah,cl           ; 1 char: get the character total.
  295.         mov     ch,cl           ; Save here too (need 'cl' for shift).
  296.         and     ah,0C0H         ; Turn off all but the two high order bits.
  297.         mov     cl,6
  298.         shr     ah,cl           ; Shift them into the low order position.
  299.         mov     cl,ch
  300.         add     ah,cl           ; Add it to the old bits.
  301.         and     ah,3FH          ; Turn off the two high order bits.  (MOD 64)
  302.         add     ah,' '          ; Add a space so the number is printable.
  303.         mov     [bx],ah         ; Put in the packet.
  304.         inc     bx              ; Point to next char.
  305.         call    spkout          ; send it
  306.         jnc     spackz          ; Add EOL char.
  307.         jmp     spackq          ; bad send
  308. spacky: mov     byte ptr[bx],0  ; null, to determine end of buffer.
  309.         push    bx              ; Don't lose our place.
  310.         mov     bx,pktptr       ; First checksummed character.
  311.         inc     bx              ; skip SOH
  312.         call    crcclc          ; Calculate the CRC.
  313.         pop     bx
  314.         push    cx              ; save the crc
  315.         mov     ax,cx           ; Manipulate it here.
  316.         and     ax,0F000H       ; Get 4 highest bits.
  317.         mov     cl,4
  318.         shr     ah,cl           ; Shift them over 4 bits.
  319.         add     ah,' '          ; Make printable.
  320.         mov     [bx],ah         ; Add to buffer.
  321.         inc     bx
  322.         pop     cx              ; Get back checksum value.
  323.         call    spkout          ; send it
  324.         jnc     spackx
  325.         jmp     spackq          ; bad send
  326. spackx: push    cx              ; Save it for now.
  327.         and     cx,0FC0H        ; Get bits 6-11.
  328.         mov     ax,cx
  329.         mov     cl,6
  330.         shr     ax,cl           ; Shift them bits over.
  331.         add     al,' '          ; Make printable.
  332.         mov     [bx],al         ; Add to buffer.
  333.         inc     bx
  334.         mov     ah,al
  335.         call    spkout          ; send it
  336.         pop     cx              ; Get back the original.
  337.         jc      spackq          ; c = bad send
  338.         and     cx,003FH        ; Get bits 0-5.
  339.         add     cl,' '          ; Make printable.
  340.         mov     [bx],cl         ; Add to buffer.
  341.         inc     bx
  342.         mov     ah,cl
  343.         call    spkout          ; send it
  344.         jnc     spackz
  345. spackq: RET                     ; bad send, do ret to caller of spack
  346. spackz: mov     ah,trans.seol   ; Get the EOL the other host wants.
  347.         mov     [bx],ah         ; Put eol
  348.         inc     bx
  349.         call    deblin          ; do debug display (while it's still our turn)
  350.         cmp     flags.debug,0   ; In debug mode?
  351.         jne     spackz0         ; ne = yes
  352.         test    flags.capflg,logpkt ; log packets?
  353.         jz      spackz1         ; z = no
  354. spackz0:cmp     linecnt,0       ; anything on current line?
  355.         je      spackz1         ; e = no
  356.         mov     dx,offset crlf  ; finish line with cr/lf
  357.         call    captdol         ;  to log file
  358. spackz1:mov     ah,trans.seol   ; recover EOL
  359.         call    spkout          ; send it
  360.         jnc     spackz2
  361.         jmp     spackq          ; bad send
  362. spackz2:
  363.         mov     ax,spkcnt       ; number of bytes sent in this packet
  364.         add     fsta.psbyte,ax  ; total bytes sent
  365.         adc     fsta.psbyte+2,0 ; propagate carry to high word
  366.         call    chkcon          ; check console for user interrupts
  367.          nop                    ;  no action on plain rets
  368.          nop
  369.          nop
  370.         jmp     rskp            ; return successfully
  371. SPKT    ENDP
  372.  
  373. spkout: push    ax              ; send char in ah out the serial port
  374.         push    bx              ; return carry clear if success
  375.         push    cx
  376.         push    dx
  377.         mov     tmp,1           ; retry counter
  378. spkour: call    outchr          ; serial port transmitter procedure
  379.          jmp    short spkoux    ; bad send, retry
  380.          nop
  381.         inc     spkcnt          ; count number of bytes sent in this packet
  382.         pop     dx
  383.         pop     cx
  384.         pop     bx
  385.         pop     ax
  386.         clc                     ; carry clear for good send
  387.         ret
  388. spkoux: cmp     tmp,5           ; done 5 attempts on this char?
  389.         jge     spkoux1         ; ge = yes, fail the sending
  390.         inc     tmp
  391.         push    ax
  392.         mov     ax,10           ; wait 10 milliseconds
  393.         call    pcwait
  394.         pop     ax
  395.         jmp     short spkour    ; retry
  396. spkoux1:pop     dx              ; failed to send char
  397.         pop     cx
  398.         pop     bx
  399.         pop     ax
  400.         stc                     ; set carry for bad send
  401.         ret
  402.  
  403. ; Calculate the CRC of the null-terminated string whose address is in BX.
  404. ; Returns the CRC in CX.  Destroys BX and AX.
  405. ; The CRC is based on the SDLC polynomial: x**16 + x**12 + x**5 + 1.
  406. ; By Edgar Butt  28 Oct 1987 [ebb].
  407. crcclc: push    dx
  408.         mov     dx,0                ; Initial CRC value is 0
  409.         mov     cl,4                ; Load shift count
  410. crc0:   mov     ah,[bx]             ; Get the next char of the string
  411.         cmp     ah,0                ; If null, then we're done
  412.         je      crc1
  413.         inc     bx
  414.         xor     dl,ah               ; XOR input with lo order byte of CRC
  415.         mov     ah,dl               ; Copy it
  416.         shl     ah,cl               ; Shift copy
  417.         xor     ah,dl               ; XOR to get quotient byte in ah
  418.         mov     dl,dh               ; High byte of CRC becomes low byte
  419.         mov     dh,ah               ; Initialize high byte with quotient
  420.         mov     al,0
  421.         shr     ax,cl               ; Shift quotient byte
  422.         xor     dl,ah               ; XOR (part of) it with CRC
  423.         shr     ax,1                ; Shift it again
  424.         xor     dx,ax               ; XOR it again to finish up
  425.         jmp     short crc0
  426. crc1:   mov     cx,dx               ; Return it in CX
  427.         pop     dx
  428.         ret
  429.  
  430. ; Receive_Packet
  431. ; This routine waits for a packet arrive from the host.  It reads
  432. ; chars until it finds a SOH.
  433. ; Returns
  434. ;       PACK.SEQNUM - Packet sequence number
  435. ;       PACK.DATLEN - Number of data characters
  436. ;       DATA array  - data in packet
  437. ;       AH -  packet type (letter code)
  438. ; Packet construction areas:
  439. ;       Prolog (8 bytes+2 nulls)        null    Data    null  Data     null
  440. ;+----------------------------------------+---------------+---------------+
  441. ;| SOH,LEN,SEQ,TYPE,Xlen(2-3),Xlen chksum | packet's data | chksum,EOL,HS |
  442. ;+----------------------------------------+---------------+---------------+
  443. ; where Xlen is 2 byte (Long) or 3 byte (Extra Long) count of bytes to follow.
  444.  
  445. RPACK   PROC    NEAR
  446.         call    rcvdeb                  ; setup debug banner, if needed.
  447.         mov     fairflg,0               ; set fairness flag
  448.         mov     pktptr,offset prolog   ; where to place packet prolog material
  449.         mov     bx,pktptr               ; bx = debug buffer pointer for new data
  450.         mov     rpkcnt,0             ; number of bytes received in this packet
  451.         mov     ax,0                  ; most recently read char, initialize it
  452.         push    bx
  453.         mov     bl,flags.cxzflg         ; Remember original value
  454.         mov     tmpflg,bl               ; Store it here
  455.         mov     parmsk,0ffh             ; parity mask, assume 8 bit data
  456.         mov     bx,portval
  457.         cmp     [bx].parflg,parnon      ; parity is none?
  458.         pop     bx
  459.         je      rpack0                  ; e = none
  460.         mov     parmsk,07fh             ; else strip parity (8th) bit
  461. rpack0: call    deblin                  ; debug, show chars received thus far
  462.         mov     word ptr prolog,0       ; clear prolog and data fields
  463.         mov     word ptr prolog+2,0
  464.         mov     word ptr prolog+4,0
  465.         mov     word ptr prolog+6,0
  466.         mov     word ptr data,0
  467.         mov     pktptr,offset prolog  ; where to place packet prolog material
  468.         mov     bx,pktptr             ; bx = debug buffer pointer for new data
  469.         mov     status,stat_suc         ; assume success
  470.         call    inchr                   ; Get a character. SOH
  471.          jmp    rpack0a         ; failure (eol, timeout, user intervention)
  472.          nop
  473. rpack0b:mov     byte ptr[bx],al ; store char in buffer
  474.         inc     bx
  475.         cmp     al,trans.rsoh   ; Is the char the start of header char?
  476.         jne     rpack0          ; ne = no, go until it is.
  477.         jmp     rpack1          ; got the SOH char from the port
  478. rpack0a:jc      rpack0b         ; c = hit eol from prev packet, restart
  479.         jmp     rpack6          ; timeout or user intervention
  480. rpack1: mov     pktptr,offset prolog    ; if we got here from below
  481.         mov     bx,pktptr               ; debug pointer
  482.         mov     byte ptr[bx],al ; store SOH in buffer
  483.         inc     bx
  484.         mov     status,stat_suc ; say success, in case rescanning for pkt.
  485.         call    inchr           ; Get a character. LEN
  486.          jmp    rpack4          ; failure
  487.          nop
  488.         mov     byte ptr[bx],al ; store LEN in buffer
  489.         inc     bx
  490.         mov     ah,0
  491.         cmp     al,trans.rsoh   ; Is the char the start of header char?
  492.         jne     rpack1e         ; ne = no
  493.         jmp     rpack7          ; yes, start over
  494. rpack1e:mov     chksum,ax       ; start the checksum
  495.         sub     al,20h          ; unchar() to binary
  496.         mov     pack.datlen,ax  ; Save the data count (byte)
  497.         call    inchr           ; Get a character. SEQ
  498.          jmp    rpack4          ; failure
  499.          nop
  500.         mov     byte ptr[bx],al ; store SEQ in buffer
  501.         inc     bx
  502.         cmp     al,trans.rsoh   ; Is the char the start of header char?
  503.         jz      rpack1          ; nz = yes, then go start over.
  504.         mov     ah,0
  505.         add     chksum,ax
  506.         sub     al,' '          ; Get the real packet number.
  507.         mov     ah,0
  508.         mov     pack.seqnum,ax  ; Save the packet number. SEQ
  509.         call    inchr           ; Get a character. TYPE
  510.          jmp    rpack4          ; failure
  511.         mov     byte ptr[bx],al ; store TYPE in buffer
  512.         inc     bx
  513.         cmp     al,trans.rsoh   ; Is the char the start of header char?
  514.         jz      rpack1          ; nz = yes, then go start over.
  515.         mov     pktype,al       ; Save the message type
  516.         mov     ah,0
  517.         add     chksum,ax       ; Add it to the checksum.
  518.         push    bx
  519.         mov     bx,portval      ; Point to current port structure
  520.         cmp     [bx].ecoflg,0   ; Is the host echoing?
  521.         pop     bx
  522.         jne     rpak11          ; No, packets not echoed
  523.         cmp     al,prvtyp       ; Packet type same as last sent?
  524.         jne     rpak11          ; ne = no
  525.         mov     prvtyp,0        ; clear to respond to next packet
  526.         jmp     rpack0          ; Yes, chuck echoed packet
  527. rpak11: call    getlen          ; get complicated data length (reg, lp, elp)
  528.                                 ; into  pack.datlen and kind into pack.lentyp
  529.                                 ; carry set if error
  530.         jnc     rpack1d         ; nc = long packet checksum is ok
  531.         or      status,stat_chk ; say bad checksum
  532.         jmp     rpack4          ; checksum failure
  533. rpack1d:
  534. ; Start of change.
  535. ; Now determine block check type for this packet.  Here we violate the layered
  536. ; nature of the protocol by inspecting the packet type in order to detect when
  537. ; the two sides get out of sync.  Two heuristics allow us to resync here:
  538. ;   a. I and S packets always has a type 1 checksum.
  539. ;   b. A NAK never contains data, so its block check type is seqnum1.
  540.         cmp     prolog+3,'S'    ; Is this an "S" packet?
  541.         jne     rpk0            ; ne = no.
  542.         mov     trans.chklen,1  ; S packets use one byte checksums
  543.         jmp     rpk3
  544. rpk0:   cmp     prolog+3,'I'    ; I packets are like S packets
  545.         jne     rpk1
  546.         mov     trans.chklen,1  ; I packets use one byte checksums
  547.         jmp     rpk3
  548. rpk1:   cmp     prolog+3,'N'    ; Is this a NAK?
  549.         jne     rpk3            ; ne = no.
  550.         cmp     pack.datlen,1   ; NAK, get length of data + chklen
  551.         jb      rpk1a           ; b = impossible length
  552.         cmp     pack.datlen,3   ; longest NAK (3 char checksum)
  553.         jbe     rpk2            ; be = possible
  554. rpk1a:  or      status,stat_ptl ; status = bad length
  555.         jmp     rpack4          ;  ret on impossible length
  556. rpk2:   mov     ax,pack.datlen
  557.         mov     trans.chklen,al ; remainder must be checksum type for NAK.
  558. rpk3:   mov     ax,pack.datlen  ; get length of data + chksum
  559.         sub     al,trans.chklen ; minus checksum length, for all packets
  560.         sbb     ah,0            ; propagate borrow
  561.         mov     pack.datlen,ax  ; store apparent length of data field
  562. ; End of change.
  563. ; now, for long packets we start the real data (after the extended byte
  564. ; count 3 or 4 bytes) at offset data and thus the checksumming starts
  565. ; such packets a few bytes earlier. [jrd]
  566.         push    si
  567.         push    di
  568.         push    cx
  569.         mov     di,offset data-1
  570.         mov     si,offset prolog
  571.         mov     pktptr,offset data
  572.         cmp     pack.lentyp,0   ; long packets?
  573.         jne     rpk5            ; ne = no
  574.         mov     cx,7            ; seven bytes mark...type, xl,xl,xlchk
  575.         add     si,6
  576.         jmp     rpk7
  577. rpk5:   cmp     pack.lentyp,1   ; extra long packets?
  578.         jne     rpk6            ; ne = no
  579.         mov     cx,8            ; extra long packets, no movement
  580.         add     si,7
  581.         jmp     rpk7
  582. rpk6:   add     si,3            ; regular packets, slide by four bytes
  583.         mov     cx,4            ; number of bytes to move
  584. rpk7:   jcxz    rpk8            ; no movement needed
  585.         sub     pktptr,cx       ; pktptr=new offset of prolog section
  586.         push    es              ; save es
  587.         push    ds
  588.         pop     es              ; set es to datas segment
  589.         std                     ; move backward
  590.         rep     movsb           ; move the protocol header, cx times
  591.         pop     es
  592.         cld                     ; reset direction flag to normal
  593. rpk8:   pop     cx
  594.         pop     di
  595.         pop     si
  596.         mov     dx,pack.datlen  ; length of data field, excl LP header
  597.         mov     chrcnt,dx
  598.         mov     dx,trans.rlongp ; longest packet we can receive
  599.         sub     dl,trans.chklen ; minus checksum length
  600.         sbb     dh,0            ; propagate borrow
  601.         cmp     pack.lentyp,3   ; Regular Packet?
  602.         jne     rpk8a           ; ne = no
  603.         sub     dx,2            ; minus SEQ, TYPE for regular packets
  604. rpk8a:  cmp     dx,pack.datlen  ; is data field too long?
  605.         jae     rpk8b           ; ae = not too big
  606.         or      status,stat_ptl ; failure status, packet too long
  607.         jmp     rpack4          ; too big, quit now
  608. rpk8b:  mov     bx,offset data  ; Point to the data buffer.
  609.  
  610.                                 ; Get DATA field characters
  611. rpack2: dec     chrcnt          ; # data chars
  612.         js      rpack3          ; s = exhausted data, go get the checksum.
  613.         call    inchr           ; Get a character into al. DATA
  614.          jmp    rpack4          ; control-c, timeout (out of data), eol
  615.          nop
  616.         mov     byte ptr[bx],al ; Put the char into the packet.
  617.         inc     bx              ; Point to the next character.
  618.         cmp     al,trans.rsoh   ; Is the char the start of header char?
  619.         jnz     rpak2b          ; nz = no
  620.         jmp     rpack7          ; yes, then go start over.
  621. rpak2b: mov     ah,0
  622.         add     chksum,ax
  623.         and     chksum,0fffh    ; keep only lower 12 bits
  624.         jmp     rpack2          ; Go get another.
  625.  
  626. rpack3: call    inchr           ; Get a character. Start Checksum bytes
  627.          jmp    rpack4          ; failed
  628.          nop
  629.         mov     byte ptr[bx],al ; place to store checksum, EOL, HS for debug
  630.         inc     bx              ; point at next slot
  631.         cmp     al,trans.rsoh   ; Is the char the start of header char?
  632.         jne     rpk3x           ; ne = no
  633.         jmp     rpack7          ; yes, then go start over.
  634. rpk3x:  sub     al,' '          ; Turn the char back into a number.
  635.         mov     cx,chksum       ; current checksum
  636.         cmp     trans.chklen,2  ; What checksum length is in use.
  637.         je      rpackx          ; e = Two character checksum.
  638.         jg      rpacky          ; g = Three character CRC.
  639.         shl     cx,1            ; put two highest digits of al into ah
  640.         shl     cx,1
  641.         and     ch,3            ; want just those two bits
  642.         shr     cl,1            ; put al back in place
  643.         shr     cl,1
  644.         add     cl,ch           ; add two high bits to earlier checksum
  645.         and     cl,03fh         ; chop to lower 6 bits (mod 64)
  646.         cmp     cl,al           ; computed vs received checksum byte (binary)
  647.         je      rpk3xa          ; e = equal, so finish up.
  648.         or      status,stat_chk ; say checksum failure
  649. rpk3xa: jmp     rpack4
  650.  
  651. rpack7: call    deblin          ; dump debugging information so far
  652.         jmp     rpack1          ; For the jump out of range.
  653.  
  654. rpacky: mov     tmp,al          ; Save value from packet here.
  655.         push    bx              ; Three character CRC.
  656.         mov     cx,[bx-1]       ; save checksum char and next
  657.         mov     temp,cx
  658.         mov     word ptr[bx-1],0 ; put null at end of Data field for crc
  659.         mov     bx,pktptr       ; Where data for CRC is.
  660.         inc     bx              ; skip SOH
  661.         call    crcclc          ; Calculate the CRC and put into CX.
  662.         pop     bx
  663.         mov     ax,temp
  664.         mov     [bx-1],ax       ; restore char pair from above
  665.         mov     ah,ch           ; cx = 16 bit binary CRC of rcv'd data
  666.         and     ah,0f0h         ; Manipulate it here.
  667.         shr     ah,1
  668.         shr     ah,1            ; Get 4 highest bits.
  669.         shr     ah,1
  670.         shr     ah,1            ; Shift them over 4 bits.
  671.         cmp     ah,tmp          ; Is what we got == what we calculated?
  672.         je      rpky1           ; e = yes
  673.         or      status,stat_chk ; checksum failure
  674. rpky1:  call    inchr           ; Get next character of checksum.
  675.          jmp    rpack4          ; Failed.
  676.          nop
  677.         mov     byte ptr[bx],al ; put into buffer for debug
  678.         inc     bx
  679.         cmp     al,trans.rsoh   ; Restarting?
  680.         je      rpack7          ; e = yes
  681.         sub     al,' '          ; Get back real value.
  682. rpackx: mov     tmp,al          ; Save here for now.
  683.         push    cx              ; Two character checksum.
  684.         and     cx,0FC0H        ; Get bits 6-11.
  685.         mov     ax,cx
  686.         mov     cl,6
  687.         shr     ax,cl           ; Shift them bits over.
  688.         pop     cx              ; Get back the original.
  689.         cmp     al,tmp          ; Are they equal?
  690.         je      rpkx1           ; yes
  691.         or      status,stat_chk ; checksum failure
  692. rpkx1:  call    inchr           ; Get last character of checksum.
  693.          jmp    rpack4          ; Failed.
  694.          nop
  695.         mov     byte ptr[bx],al ; put into buffer for debug
  696.         inc     bx
  697.         cmp     al,trans.rsoh   ; Restarting?
  698.         je      rpack7          ; e = yes
  699.         sub     al,' '          ; Get back real value.
  700.         and     cx,003FH        ; Get bits 0-5.
  701.         cmp     al,cl           ; Do the last chars match?
  702.         je      rpack4          ; e = yes
  703.         or      status,stat_chk ; say checksum failure
  704.  
  705. rpack4: test    status,stat_tmo ; timeout?
  706.         jnz     rpack6          ; nz = yes
  707.         test    status,stat_eol ; premature eol?
  708.         jnz     rpack4c         ; nz = yes, try handshake
  709.         call    inchr           ; get eol char (ok = ret with carry set)
  710.          jnc    rpack6          ; nc = timeout or user intervention
  711.          nop
  712.         cmp     bx,offset data+maxpack+7        ; filled debug buffer yet?
  713.         ja      rpack4e         ; a = yes
  714.         mov     byte ptr[bx],al ; put into buffer for debug
  715.         inc     bx
  716. rpack4e:cmp     al,trans.rsoh   ; soh already?
  717.         jne     rpack4a         ; ne = no
  718.         jmp     rpack7          ; yes
  719. rpack4a:and     status,not stat_eol ; desired eol is not an error
  720. rpack4c:push    bx              ; test for line turn char, if handshaking
  721.         mov     bx,portval
  722.         mov     ah,[bx].hands   ; get desired handshake char
  723.         cmp     [bx].hndflg,0   ; doing half duplex handshaking?
  724.         pop     bx
  725.         je      rpack6          ; e = no
  726.         mov     tmp,ah          ; keep it here
  727.         call    inchr           ; get handshake char
  728.          jnc    rpack5          ; nc = timeout or user intervention
  729.          nop
  730.         and     status,not stat_eol     ; ignore unexpected eol status here.
  731.         cmp     bx,offset data+maxpack+7        ; filled debug buffer yet?
  732.         ja      rpack4f         ; a = yes
  733.         mov     byte ptr[bx],al ; put into buffer for debug
  734.         inc     bx
  735. rpack4f:cmp     al,trans.rsoh   ; soh already?
  736.         jne     rpack4d         ; ne = no
  737.         jmp     rpack7          ; yes, do debug display and start over
  738. rpack4d:cmp     al,tmp          ; compare received char with handshake
  739.         jne     rpack4c         ; ne = not handshake, try again til timeout
  740. rpack5: and     status,not stat_tmo     ; ignore timeouts on handshake char
  741.  
  742. rpack6: call    deblin          ; do debug display
  743.         cmp     flags.debug,0   ; In debug mode?
  744.         jne     rpack6a         ; ne = yes
  745.         test    flags.capflg,logpkt ; log packets?
  746.         jz      rpack6b         ; z = no
  747. rpack6a:cmp     linecnt,0       ; anything on current line?
  748.         je      rpack6b         ; e = no
  749.         mov     dx,offset crlf  ; finish line with cr/lf
  750.         call    captdol         ;  to log file
  751.  
  752. rpack6b:call    chkcon          ; check console for user interrupt
  753.          nop
  754.          nop
  755.          nop
  756.         test    status,stat_tmo ; did a timeout get us here?
  757.         jz      rpack6c         ; z = no
  758.         mov     pktype,'T'      ; yes, say 'T' type packet (timeout)
  759. rpack6c:mov     bl,tmpflg       ; flags before rpack began
  760.         cmp     bl,flags.cxzflg ; did flags change?
  761.         je      rpack6e         ; e = no
  762.         cmp     flags.cxzflg,'C'; did user type contol-C?
  763.         je      rpack6d         ; e = yes
  764.         cmp     flags.cxzflg,'E'; protocol exit request?
  765.         jne     rpack6e         ; ne = no
  766.         mov     bx,offset cemsg ; user intervention message for error packet
  767.         call    errpack         ; send error message
  768. rpack6d:mov     pack.state,'A'  ; and move to abort state
  769.         call    intmsg          ; show interrupt msg for control-C-E
  770.  
  771. rpack6e:mov     ax,rpkcnt       ; number of bytes received in this packet
  772.         add     fsta.prbyte,ax  ; total received bytes
  773.         adc     fsta.prbyte+2,0 ; propagate carry to high word
  774.         add     fsta.prpkt,1    ; count received packet
  775.         adc     fsta.prpkt+2,0  ;  ripple carry
  776.         mov     ah,pktype       ; return packet type in ah
  777.         cmp     status,stat_suc ; successful so far?
  778.         jne     rpack6x         ; ne = no
  779.         jmp     rskp            ; success exit
  780. rpack6x:ret                     ; failure exit
  781.  
  782. RPACK   ENDP
  783.  
  784. ; Check Console (keyboard). Ret if "action" chars: cr for forced timeout,
  785. ; Control-E for force out Error packet, Control-C for quit work now.
  786. ; Return rskp on Control-X and Control-Z as these are acted upon by higher
  787. ; layers. Consume and ignore anything else.
  788. chkcon: call    isdev           ; is stdin a device and not a disk file?
  789.         jnc     chkco5          ; nc = no, a disk file so do not read here
  790.         mov     dl,0ffh
  791.         mov     ah,dconio       ; read console
  792.         int     dos
  793.         jz      chkco5          ; z = nothing there
  794.         cmp     al,cr           ; carriage return?
  795.         je      chkco3          ; e = yes, simulate timeout
  796.         cmp     al,'C'-40h      ; Control-C?
  797.         je      chkco1          ; e = yes
  798.         cmp     al,'E'-40h      ; Control-E?
  799.         je      chkco1          ; e = yes
  800.         cmp     al,'X'-40h      ; Control-X?
  801.         je      chkco4          ; e = yes
  802.         cmp     al,'Z'-40h      ; Control-Z?
  803.         je      chkco4          ; record it, take no immmediate action here
  804.         cmp     al,0            ; scan code being returned?
  805.         jne     chkcon          ; ne = no
  806.         mov     ah,dconio       ; read and discard second byte
  807.         mov     dl,0ffh
  808.         int     dos
  809.         jmp     chkcon          ; else unknown, read any more
  810. chkco1: add     al,40h          ; Make Control-C-E printable.
  811.         mov     flags.cxzflg,al ; Remember what we saw.
  812. chkco2: or      status,stat_int ; interrupted
  813.         ret                     ; act   now
  814. chkco3: or      status,stat_tmo ; cr simulates timeout
  815.         ret                     ; act   now
  816. chkco4: add     al,40h          ; make control-X-Z printable
  817.         mov     flags.cxzflg,al ; put into flags
  818.         jmp     rskp            ; do not act on them here
  819. chkco5: cmp     flags.cxzflg,'C'; control-C intercepted elsewhere?
  820.         je      chkco2          ; e = yes
  821.         jmp     rskp            ; else say no immediate action needed
  822.  
  823.  
  824. getlen  proc    near            ; compute packet length for short & long types
  825.                                 ; returns length in pack.datlen and length
  826.                                 ; type (0, 1, 3) in pack.lentyp
  827.                                 ; returns length of  data + checksum
  828.         mov     ax,pack.datlen  ; LEN from packet's second byte
  829.         xor     ah,ah           ; clear unused high byte
  830.         cmp     al,3            ; regular packet has 3 or larger here
  831.         jb      getln0          ; b = long packet
  832.         sub     pack.datlen,2   ; minus SEQ and TYPE = DATA + CHKSUM
  833.         mov     pack.lentyp,3   ; store assumed length type (3 = regular)
  834.         clc                     ; clear carry for success
  835.         ret
  836.  
  837. getln0: push    cx              ; counter for number of length bytes
  838.         mov     pack.lentyp,0   ; store assumed length type 0 (long)
  839.         mov     cx,2            ; two base-95 digits
  840.         cmp     al,0            ; is this a type 0 (long packet)?
  841.         je      getln5          ; e = yes, go find & check length data
  842. getln1: mov     pack.lentyp,1   ; store length type (1 = extra long)
  843.         mov     cx,3            ; three base 95 digits
  844.         cmp     al,1            ; is this a type 1 (extra long packet)?
  845.         je      getln5          ; e = yes, go find & check length data
  846.         pop     cx
  847.         stc                     ; set carry bit to say error (unkn len code)
  848.         ret
  849. getln5:                         ; chk header chksum and recover binary length
  850.         push    dx              ; save working reg
  851.         xor     ax,ax           ; clear length accumulator, low part
  852.         mov     pack.datlen,ax  ; clear final length too
  853. getln7: xor     dx,dx           ; ditto, high part
  854.         mov     ax,pack.datlen  ; length to date
  855.         mul     ninefive        ; multiply accumulation (in ax) by 95
  856.         mov     pack.datlen,ax  ; save results
  857.         push    cx
  858.         call    inchr           ; read another serial port char into al
  859.          nop                    ; should do something here about failures
  860.          nop
  861.          nop
  862.         pop     cx
  863.         mov     ah,0
  864.         mov     byte ptr[bx],al ; store in buffer
  865.         inc     bx
  866.         add     chksum,ax
  867.         sub     al,20h          ; subtract space, apply unchar()
  868.         add     pack.datlen,ax  ; add to overall length count
  869.         loop    getln7          ; cx preset earlier for type 0 or type 1
  870.         mov     dx,chksum       ; get running checksum
  871.         shl     dx,1            ; get two high order bits into dh
  872.         shl     dx,1
  873.         and     dh,3            ; want just these two bits
  874.         shr     dl,1            ; put low order part back
  875.         shr     dl,1
  876.         add     dl,dh           ; add low order byte to two high order bits
  877.         and     dl,03fh         ; chop to lower 6 bits (mod 64)
  878.         add     dl,20h          ; apply tochar()
  879.         push    dx
  880.         call    inchr           ; read another serial port char
  881.          nop
  882.          nop
  883.          nop
  884.         pop     dx
  885.         mov     ah,0
  886.         mov     byte ptr[bx],al ; store in buf for debug
  887.         inc     bx
  888.         add     chksum,ax
  889.         cmp     dl,al           ; our vs their checksum, same?
  890.         pop     dx              ; unsave regs (preserves flags)
  891.         pop     cx
  892.         je      getln9          ; e = checksums match, success
  893.         or      status,stat_chk ; checksum failure
  894.         stc                     ; else return carry set for error
  895.         ret
  896. getln9: clc                     ; clear carry (say success)
  897.         ret
  898. getlen  endp
  899.  
  900. ; Get char from serial port into al, with timeout and console check.
  901. ; Ret carry clear if timeout or console char, Ret carry set if EOL seen,
  902. ; Rskp on other port chars. Fairflg allows occassional reads from console
  903. ; before looking at serial port, to avoid latchups.
  904. inchr:  mov     timeit,0        ; reset timeout flag (do each char separately)
  905.         push    bx              ; save a reg
  906.         cmp     fairflg,maxpack ; look at console first every now and then
  907.         jbe     inchr1          ; be = not console's turn yet
  908.         call    chkcon          ; check console
  909.          jmp    inchr5          ; got cr or control-c/e input
  910.          nop
  911.         mov     fairflg,0       ; reset fairness flag for next time
  912. inchr1: call    prtchr          ; Is there a serial port character to read?
  913.          jmp    inchr6          ; Got one (in al); else does rskp.
  914.          nop
  915.         call    chkcon          ; check console
  916.          jmp    inchr5          ; got cr or control-c/e input
  917.          nop
  918. inchr2: cmp     flags.timflg,0  ; Are timeouts turned off?
  919.         je      inchr1          ; e = yes, just check for more input.
  920.         cmp     trans.stime,0   ; Doing time outs?
  921.         je      inchr1          ; e = no, just go check for more input.
  922.         push    cx              ; save regs
  923.         push    dx              ; Stolen from Script code.
  924.         cmp     timeit,0        ; have we gotten time of day for first fail?
  925.         jne     inchr4          ; ne = yes, just compare times
  926.         mov     ah,gettim       ; get DOS time of day
  927.         int     dos             ; ch = hh, cl = mm, dh = ss, dl = 0.01 sec
  928.         xchg    ch,cl           ; get ordering of low byte = hours, etc
  929.         mov     word ptr rptim,cx ; hours and minutes
  930.         xchg    dh,dl
  931.         mov     word ptr rptim+2,dx ; seconds and fraction
  932.         mov     bl,trans.stime  ; our desired timeout interval (seconds)
  933.         mov     bh,0            ; one byte's worth
  934.         mov     temp,bx         ; work area
  935.         mov     bx,2            ; start with seconds field
  936. inchr3: mov     ax,temp         ; desired timeout interval, working copy
  937.         add     al,rptim[bx]    ; add current tod digit interval
  938.         adc     ah,0
  939.         xor     dx,dx           ; clear high order part thereof
  940.         div     sixzero         ; compute number of minutes or hours
  941.         mov     temp,ax         ; quotient, for next time around
  942.         mov     rptim[bx],dl    ; put normalized remainder in timeout tod
  943.         dec     bx              ; look at next higher order time field
  944.         cmp     bx,0            ; done all time fields?
  945.         jge     inchr3          ; ge = no
  946.         cmp     rptim[0],24     ; normalize hours
  947.         jl      inchr3a         ; l = not 24 hours or greater
  948.         sub     rptim[0],24     ; discard part over 24 hours
  949. inchr3a:mov     timeit,1        ; say have tod of timeout
  950.  
  951. inchr4: mov     ah,gettim       ; compare present tod versus timeout tod
  952.         int     dos             ; get the time of day
  953.         sub     ch,rptim        ; hours difference, ch = (now - timeout)
  954.         je      inchr4b         ; e = same, check mmss.s
  955.         jl      inchr4d         ; l = we are early
  956.         cmp     ch,12           ; hours difference, large or small?
  957.         jge     inchr4d         ; ge = we are early
  958.         jl      inchr4c         ; l = we are late, say timeout
  959. inchr4b:cmp     cl,rptim+1      ; minutes, hours match
  960.         jb      inchr4d         ; b = we are early
  961.         ja      inchr4c         ; a = we are late
  962.         cmp     dh,rptim+2      ; seconds, hours and minutes match
  963.         jb      inchr4d         ; b = we are early
  964.         ja      inchr4c         ; a = we are late
  965.         cmp     dl,rptim+3      ; hundredths of seconds, hhmmss match
  966.         jb      inchr4d         ; b = we are early
  967. inchr4c:or      status,stat_tmo ; say timeout
  968.         pop     dx
  969.         pop     cx
  970.         jmp     inchr5          ; timeout exit
  971. inchr4d:pop     dx
  972.         pop     cx
  973.         jmp     inchr1          ; not timed out yet
  974.  
  975. inchr5: pop     bx              ; here with console char or timeout
  976.         clc                     ; clear carry bit
  977.         ret                     ; failure
  978.  
  979. inchr6: pop     bx              ; here with char in al from port
  980.         and     al,parmsk       ; apply 7/8 bit parity mask
  981.         or      al,al           ; null char?
  982.         jnz     inchr6b         ; nz = no
  983. inchr6a:jmp     inchr           ; ignore the null, read another char
  984. inchr6b:cmp     al,del          ; ascii del byte?
  985.         je      inchr6a         ; e = yes, ignore it too
  986.         inc     rpkcnt          ; count received byte
  987.         cmp     al,trans.reol   ; eol char we want?
  988.         je      inchr7          ; e = yes, ret with carry set
  989.         jmp     rskp            ; char is in al
  990. inchr7: or      status,stat_eol ; set status appropriately
  991.         stc                     ; set carry to say eol seen
  992.         ret                     ; and return qualified failure
  993.  
  994. ; sleep for the # of seconds in al
  995. ; Preserve all regs. Added console input forced timeout 21 March 1987 [jrd]
  996. sleep   proc    near
  997.         push    ax
  998.         push    cx
  999.         push    dx
  1000.         push    ax              ; save argument
  1001.         mov     ah,gettim       ; DOS tod (ch=hh, cl=mm, dh=ss, dl=.s)
  1002.         int     dos             ; get current time
  1003.         pop     ax              ; restore desired # of seconds
  1004.         add     dh,al           ; add # of seconds
  1005. sleep1: cmp     dh,60           ; too big for seconds?
  1006.         jb      sleep2          ; no, keep going
  1007.         sub     dh,60           ; yes, subtract a minute's overflow
  1008.         inc     cl              ; and add one to minutes field
  1009.         cmp     cl,60           ; did minutes overflow?
  1010.         jb      sleep1          ; no, check seconds again
  1011.         sub     cl,60           ; else take away an hour's overflow
  1012.         inc     ch              ; add it back in hours field
  1013.         jmp     sleep1          ; and keep checking
  1014. sleep2: mov     time,cx         ; store desired ending time,  hh,mm
  1015.         mov     time+2,dx       ; ss, .s
  1016. sleep3: call    chkcon          ; check console for user timeout override
  1017.          jmp    short sleep5    ; have override
  1018.          nop                    ;  three bytes for rskp
  1019.         mov     ah,gettim       ; get time
  1020.         int     dos             ; from dos
  1021.         sub     ch,byte ptr time+1 ; hours difference, ch = (now - timeout)
  1022.         je      sleep4          ; e = hours match, check mmss.s
  1023.         jl      sleep3          ; l = we are early
  1024.         cmp     ch,12           ; hours difference, large or small?
  1025.         jge     sleep3          ; ge = we are early
  1026.         jl      sleep5          ; l = we are late, exit now
  1027. sleep4: cmp     cl,byte ptr time ; check minutes, hours match
  1028.         jb      sleep3          ; b = we are early
  1029.         ja      sleep5          ; a = over limit, time to exit
  1030.         cmp     dx,time+2       ; check seconds and fraction, hhmm match
  1031.         jb      sleep3          ; b = we are early
  1032. sleep5: pop     dx
  1033.         pop     cx
  1034.         pop     ax
  1035.         ret
  1036. sleep   endp
  1037.                                 ; Packet Debug display routines
  1038. rcvdeb: cmp     flags.debug,0   ; In debug mode?
  1039.         jne     rcvde1          ; ne = yes
  1040.         test    flags.capflg,logpkt ; log packets?
  1041.         jnz     rcvde1          ; e = yes
  1042.         ret                     ; no
  1043. rcvde1: mov     debflg,'R'      ; say receiving
  1044.         jmp     deb1
  1045.  
  1046. snddeb: cmp     flags.debug,0   ; In debug mode?
  1047.         jne     sndde1          ; ne = yes
  1048.         test    flags.capflg,logpkt ; log packets?
  1049.         jnz     sndde1          ; yes
  1050.         ret                     ; no
  1051. sndde1: mov     debflg,'S'      ; say sending
  1052.  
  1053. deb1:   push    ax              ; Debug. Packet display.
  1054.         push    bx
  1055.         push    cx              ; save some regs.
  1056.         push    dx
  1057.         push    di
  1058.         test    flags.debug,logpkt      ; is debug active (vs just logging)?
  1059.         jz      deb1d           ; z = no, just logging
  1060.         cmp     fmtdsp,0        ; non-formatted display?
  1061.         je      deb1d           ; e = yes, skip extra line clearing
  1062.         cmp     debflg,'R'      ; receiving?
  1063.         je      deb1a           ; e = yes
  1064.         call    sppos           ; spack: cursor position
  1065.         jmp     deb1b
  1066. deb1a:  call    rppos           ; rpack: cursor position
  1067. deb1b:  call    clearl          ; clear the line
  1068.         mov     dx,offset crlf
  1069.         mov     ah,prstr        ; display
  1070.         int     dos
  1071.         call    clearl          ; clear debug line and line beneath
  1072. deb1e:  cmp     debflg,'R'      ; receiving?
  1073.         je      deb1c           ; e = yes
  1074.         call    sppos           ; reposition cursor for spack:
  1075.         jmp     deb1d
  1076. deb1c:  call    rppos           ; reposition cursor for rpack:
  1077. deb1d:  mov     dx,offset spmes ; spack: message
  1078.         cmp     debflg,'R'
  1079.         jne     deb2            ; ne = sending
  1080.         mov     dx,offset rpmes ; rpack: message
  1081. deb2:   call    captdol         ; record dollar terminated string in Log file
  1082.         mov     linecnt,7       ; number of columns used so far
  1083.         pop     di
  1084.         pop     dx
  1085.         pop     cx
  1086.         pop     bx
  1087.         pop     ax
  1088.         ret                     ; done
  1089.  
  1090. ; Display/log packet chars processed so far.
  1091. ; Displays chars from pktptr to bx, both are pointers.
  1092. ; Enter with bx = offset of next new char. All registers preserved
  1093. deblin: cmp     flags.debug,0   ; In debug mode?
  1094.         jne     debln0          ; ne = yes
  1095.         test    flags.capflg,logpkt ; log packets?
  1096.         jnz     debln0          ; nz = yes
  1097.         ret                     ; else  nothing to do
  1098. debln0: push    cx
  1099.         push    dx
  1100.         push    di
  1101.         mov     di,pktptr       ; starting place for debug analysis
  1102.         mov     cx,bx           ; place for next new char
  1103.         sub     cx,di           ; minus where we start = number chars to do
  1104.         cmp     cx,0
  1105.         jle     debln5          ; le = nothing to do
  1106. debln2: cmp     di,offset data+maxpack+10 ; end of buffer data?
  1107.         ja      debln5          ; a = all done
  1108.         push    cx              ; save loop counter
  1109.         cmp     linecnt,70
  1110.         jb      debln3          ; b = not yet, get next data char
  1111.         mov     dx,offset crlf  ; break line with cr/lf
  1112.         call    captdol         ; and in log file
  1113.         mov     linecnt,0       ; setup for next line
  1114. debln3: mov     dl,byte ptr [di]; get char
  1115.         test    dl,80h          ; high bit set?
  1116.         jz      debln3b         ; z = no
  1117.         push    dx              ; save char in dl
  1118.         mov     dl,7eh          ; show tilde char for high bit set
  1119.         call    captchr         ; record in Log file
  1120.         inc     linecnt         ; count displayed column
  1121.         cmp     linecnt,70      ; exhausted line count yet?
  1122.         jb      debln3a         ; b = not yet
  1123.         mov     dx,offset crlf  ; break line with cr/lf
  1124.         call    captdol         ; and in log file
  1125.         mov     linecnt,0       ; setup for next line
  1126. debln3a:pop     dx
  1127.         and     dl,7fh          ; get lower seven bits here
  1128. debln3b:cmp     dl,' '          ; control char?
  1129.         jae     debln4          ; ae = no
  1130.         add     dl,40h          ; uncontrollify the char
  1131.         push    dx              ; save char in dl
  1132.         mov     dl,5eh          ; show caret before control code
  1133.         call    captchr         ; record in Log file
  1134.         inc     linecnt         ; count displayed column
  1135.         cmp     linecnt,70      ; exhausted line count yet?
  1136.         jb      debln3c         ; b = not yet
  1137.         mov     dx,offset crlf  ; break line with cr/lf
  1138.         call    captdol         ; and in log file
  1139.         mov     linecnt,0       ; setup for next line
  1140. debln3c:pop     dx              ; recover char in dl
  1141.  
  1142. debln4: call    captchr         ; record char in dl in the log file
  1143.         inc     di              ; done with this char, point to next
  1144.         inc     linecnt         ; one more column used on screen
  1145.         pop     cx              ; recover loop counter
  1146.         loop    debln2          ; get next data char
  1147. debln5: pop     di
  1148.         pop     dx
  1149.         pop     cx
  1150.         ret
  1151.  
  1152. captdol proc    near            ; write dollar sign terminated string in dx
  1153.                                 ; to the capture file (Log file). [jrd]
  1154.         push    ax              ; save regs
  1155.         push    si
  1156.         mov     si,dx           ; point to start of string
  1157. captdo1:lodsb                   ; get   a byte into al
  1158.         cmp     al,'$'          ; at the end yet?
  1159.         je      captdo2         ; e = yes
  1160.         mov     dl,al
  1161.         call    captchr         ; Log the char
  1162.         jmp     short captdo1   ; repeat until dollar sign is encountered
  1163. captdo2:pop     si
  1164.         pop     ax
  1165.         ret
  1166. captdol endp
  1167.  
  1168. captcx  proc    near            ; record counted string, starts in di, count
  1169.                                 ;  is in cx. [jrd]
  1170.         jcxz    captc2          ; if count = zero, exit now
  1171.         push    ax              ; save regs
  1172.         push    cx
  1173.         push    si
  1174.         mov     si,di           ; get start address
  1175. captc1: lodsb                   ; get a char into al
  1176.         call    pktcpt          ; record it, cptchr is in msster.asm
  1177.         loop    captc1          ; do this cx times
  1178.         pop     si
  1179.         pop     cx
  1180.         pop     ax
  1181. captc2: ret
  1182. captcx  endp
  1183.  
  1184. captchr proc    near            ; record char in dl into the Log file
  1185.         push    ax
  1186.         cmp     flags.debug,0   ; debug display active?
  1187.         jz      captch1         ; z = no.
  1188.         mov     ah,conout
  1189.         int     dos             ; display char in dl
  1190. captch1:test    flags.capflg,logpkt ; logging active?
  1191.         jz      captch2         ; z = no
  1192.         mov     al,dl           ; where pktcpt wants it
  1193.         call    pktcpt          ; record the char, pktcpt is in msster.asm
  1194. captch2:pop     ax
  1195.         ret
  1196. captchr endp
  1197.  
  1198. ; Jumping to this location is like retskp.  It assumes the instruction
  1199. ;   after the call is a jmp addr.
  1200.  
  1201. RSKP    PROC    NEAR
  1202.         pop     bp
  1203.         add     bp,3
  1204.         push    bp
  1205.         ret
  1206. RSKP    ENDP
  1207.  
  1208. ; Jumping here is the same as a ret.
  1209.  
  1210. R       PROC    NEAR
  1211.         ret
  1212. R       ENDP
  1213.  
  1214. code    ends
  1215.         end
  1216.  
  1217.  
  1218.